home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
prolog
/
brklyprl.lha
/
Comp
/
herve_peephole.pl
< prev
next >
Wrap
Text File
|
1989-04-14
|
7KB
|
191 lines
/* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
/* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
% does the following modifications:
% (1) add an arg to unify structures to specify read or unknown mode
% we will make it general. If unbound, means the mode is unknown
% have to modify the write routines accordingly
% (2) add the arity to the get_structure and put_structure instructions
% (3) insert, between two unify instructions, in a list context, the
% instruction get_cdr_list, with no arguments.
% (4) fix up the treatment of metacalls
% It works in two passes:
% the first pass unroll the unify_voids, and propagates the read and
% unknown modes.
% the second pass treats the lists.
% the third pass replaces the allocates N into inits and removes most
% of the inits.
herve_peephole(Code,PCode,Link) :-
herve_first_pass(Code,ICode,[],unknown),
herve_second_pass(ICode,SCode,[],unknown),
herve_third_pass(SCode,PCode,Link).
herve_first_pass([Instr|Code],[Instr|PCode],Link,_) :-
(Instr = get_list(_); Instr = get(structure,_,_)),
!,
herve_first_pass(Code,PCode,Link,unknown).
herve_first_pass([Instr|Code],[Instr|PCode],Link,_) :-
(Instr = put_list(_); Instr = put(structure,_,_)),
!,
herve_first_pass(Code,PCode,Link,write).
herve_first_pass([unify(void,N)|Code],[unify(void,1,Mode)|PCode],Link,Mode) :-
N > 1,
!,
N1 is N - 1,
herve_first_pass([unify(void,N1)|Code],PCode,Link,Mode).
herve_first_pass([unify(Type,X)|Code],[unify(Type,X,Mode)|PCode],Link,Mode) :-
!,
herve_first_pass(Code,PCode,Link,Mode).
herve_first_pass([unify_nil|Code],[unify_nil(Mode)|PCode],Link,Mode) :-
!,
herve_first_pass(Code,PCode,Link,Mode).
% last instruction
herve_first_pass([],LastCode,LastCode,_).
% catch all case
herve_first_pass([Instr|Code],[Instr|PCode],Link,Mode) :-
!,
herve_first_pass(Code,PCode,Link,Mode).
herve_second_pass([Instr|Code],[Instr|PCode],Link,_) :-
(Instr = get_list(_); Instr = put_list(_)),
!,
skip_allocate(Code,Rest,PCode,PRest),
herve_second_pass(Rest,PRest,Link,list).
herve_second_pass([Instr|Code],[Instr|PCode],Link,_) :-
(Instr = put(structure,_,_); Instr = get(structure,_,_)),
!,
herve_second_pass(Code,PCode,Link,structure).
herve_second_pass([unify(cdr,X,Mode)|Code],PCode,Link,Context) :-
!,
PCode = [unify(variable,X,Mode)|Rest],
herve_second_pass(Code,Rest,Link,Context).
herve_second_pass([allocate(0)|Code],PCode,Link,Context) :-
!,
herve_second_pass(Code,PCode,Link,Context).
herve_second_pass([Instr|Code],[get_cdr_list(Mode),Instr|PCode],Link,list) :-
Instr = unify(_,_,Mode),
!,
herve_second_pass(Code,PCode,Link,list).
herve_second_pass([unify_nil(_)|Code],PCode,Link,structure) :-
!,
herve_second_pass(Code,PCode,Link,structure).
herve_second_pass([Instr|Code],[Instr|PCode],Link,structure) :-
Instr = unify(_,_,_),
!,
herve_second_pass(Code,PCode,Link,structure).
% last instruction
herve_second_pass([],LastCode,LastCode,_).
% catch-all case
herve_second_pass([Instr|Code],[Instr|PCode],Link,Context) :-
!,
herve_second_pass(Code,PCode,Link,Context).
skip_allocate([allocate(N),Instr|Rest],Rest,PCode,PRest) :-
!,
PCode = [allocate(N),Instr|PRest].
skip_allocate([Instr|Rest],Rest,[Instr|PRest],PRest).
% treats the allocates correctly. Replaces them by inits, and only put
% the necessary number of inits. Also look at the first occurrence of
% those variables in the remaining of the clause, and replace their
% variable annotations by value annotations.
% Rest = a list of instructions, [] terminated, corresponding to a clause
% PCode = the transformed of Rest
% Link = the link to the end of PCode
herve_third_pass(Rest,PCode,Link) :-
herve_third_pass(Rest,PCode,Link,_,[],noalloc).
% 4th argument = place holder: [PLink,N|PRest]
% PLink = location in the code for the sequence of inits
% N = size of env
% PRest = the rest of the code
% 5th argument = the list of Yvars encountered so far (before first jump)
% 6th argument = whether an allocate has been encountered so far or not
herve_third_pass([allocate(N)|Rest],PLink,Link,_,YVars,_) :- !,
herve_third_pass(Rest,PRest,Link,[PLink,N|PRest],YVars,alloc).
herve_third_pass([Instr|Rest],[Instr|PRest],Link,X,YVars,Mode) :-
Instr = unify(variable,y(N),_), !,
herve_third_pass(Rest,PRest,Link,X,[y(N)|YVars],Mode).
herve_third_pass([Instr|Rest],[Instr|PRest],Link,X,YVars,Mode) :-
Instr =.. [Name,variable,y(N)|_], !,
(Name = get; Name = put),
herve_third_pass(Rest,PRest,Link,X,[y(N)|YVars],Mode).
herve_third_pass([Instr|Rest],[Instr|PRest],Link,X,YVars,alloc) :-
(Instr = call(_,_); Instr = execute(_);
Instr = proceed; Instr = fail/0), !,
compute_inits(X,YVars,InitVars),
herve_end_third_pass(Rest,PRest,Link,InitVars).
herve_third_pass([Instr|Code],[Instr|PCode],Link,Init,YVars,Mode) :-
herve_third_pass(Code,PCode,Link,Init,YVars,Mode).
herve_third_pass([],Link,Link,_,_,_).
% Marker = pointer to the place in the code where to put the inits
% Rest = link to the end of the inits
% N = size of the environment
% YVars = list of the variables encountered before the first jump
% InitVars = list of the variables to be initialized
% does the insertion of the init code.
compute_inits([Marker,N|Rest],YVars,InitVars) :-
compute_complement(N,YVars,InitVars),
make_inits(InitVars,Inits,ILink),
Marker = Inits,
ILink = Rest.
% replace [y(1),y(2)] by [init(1),init(2)|Link]
make_inits([],Link,Link).
make_inits([y(N)|YVars],[init(N)|Inits],Link) :-
make_inits(YVars,Inits,Link).
% y(I) is in InitVars iff 1 <= I <= N and y(I) is not in YVars
compute_complement(0,_,[]) :- !.
compute_complement(N,YVars,InitVars) :-
member(y(N),YVars), !,
N1 is N - 1,
compute_complement(N1,YVars,InitVars).
compute_complement(N,YVars,[y(N)|InitVars]) :-
N1 is N - 1,
compute_complement(N1,YVars,InitVars).
% replace first encounter of a Y variable after an init from variable
% to value annotation
herve_end_third_pass([Instr|Rest],[NewInstr|PRest],Link,InitVars) :-
Instr = unify(variable,y(N),X), !,
(match_and_remove(y(N),InitVars,NewInitVars) ->
NewInstr = unify(value,y(N),X);
(NewInstr = Instr, NewInitVars = InitVars)),
herve_end_third_pass(Rest,PRest,Link,NewInitVars).
herve_end_third_pass([Instr|Rest],[NewInstr|PRest],Link,InitVars) :-
Instr =.. [Name,variable,y(N)|Tail],
(Name = get; Name = put), !,
(match_and_remove(y(N),InitVars,NewInitVars) ->
NewInstr =.. [Name,value,y(N)|Tail];
(NewInstr = Instr, NewInitVars = InitVars)),
herve_end_third_pass(Rest,PRest,Link,NewInitVars).
herve_end_third_pass([Instr|Code],[Instr|PCode],Link,InitVars) :- !,
herve_end_third_pass(Code,PCode,Link,InitVars).
herve_end_third_pass([],LastCode,LastCode,_).
% fail if 1st argument does not belong to 2nd argument
% when succeeds, the 3rd argument is the 2nd minus the first.
match_and_remove(Y,[Y|Inits],Inits) :- !.
match_and_remove(Y,[Z|Inits],[Z|NewInits]) :-
match_and_remove(Y,Inits,NewInits).